home *** CD-ROM | disk | FTP | other *** search
- PAGE 59, 132
-
- TITLE MSSET -- Set and Status commands
-
- ; Update 13 Jan 86
-
- IF1
- %OUT >> Starting pass 1
- ELSE
- %OUT >> Starting pass 2
- ENDIF
-
- public setcom, status, stat0, baudprt, escprt, prmptr, dodef
- public setcpt, docom, shomac, atoi, m7171, AutoWrap
- include msdefs.h
-
- setextra equ 250
- macmax equ 40 ; Maximum # of macros
-
- datas segment public 'datas'
-
- PUBLIC MacTab, MccTab, Force_card
-
- extrn comand:byte, flags:byte, trans:byte, cptfcb:byte, takadr:word
- extrn taklev:byte, inichk:byte, portval:word, curdsk:byte
- EXTRN Force_mono:BYTE, In_menu_mode:BYTE, Menu_file_name:BYTE
- EXTRN Reload_menu_flag:BYTE
-
- kerm LABEL BYTE
- Program_name
- db '> $'
-
- crlf db cr,lf,'$'
- crlfsp db cr,lf
- Blank db ' $'
- eqs db ' = $'
- ermes1 db '? Too many macros',cr,lf,'$'
- ermes2 db '? No room in table for macro',cr,lf,'$'
- ermes3 db '? Not confirmed',cr,lf,'$'
- ermes4 db '? No room in take stack to expand macro',cr,lf,'$'
- ermes5 db '? Not implemented',cr,lf,'$'
- erms23 db '? 0 or null scan code not allowed',cr,lf,'$' ;[jd]
- erms24 db '? Capture file already open (use close command)',cr,lf,'$'
- erms31 db '? File not found',cr,lf,'$'
- erms38 db '? Insufficient TAKE stack space to parse filename',cr,lf,'$'
- filmsg db ' File specification with optional path name$'
- filhlp db ' Input file specification for session logging$'
- macmsg db ' Macro name, followed by body of macro.',Cr,Lf
- db ' The "body of a macro" is a series of commands, separated '
- db 'by commas.',Cr,Lf
- db ' Macros are executed with the "DO macro" command.$'
- shmmsg db ' Confirm with carriage return$'
- prmmsg db ' Enter new prompt string $'
- sk1msg db ' Decimal scan code for key $'
- sk2msg db ' Redefinition string for key $'
- prterr db '? Unrecognized value',cr,lf,'$'
- unrec db 'BAUD rate is unknown$'
- defpmp db 'Definition string: $'
- esctl db 'CONTROL-$' ; [6]
- nonmsg db 'NONE$'
- delmsg db 'DELETE$'
- onmsg db 'ON'
- offmsg db 'OFF'
- Disp_msg db 'DISPLAY $'
- Display_color db 'permitted to be COLOR'
- Display_mono db 'forced to be MONOCHROME'
- tmp db ?,'$'
- sum db 0
- min db 0
- max db 0
- desta dw 0
- numerr dw 0
- numhlp dw 0
- Hold_bx DW ? ; Place to hold bx register
- Hold_di DW ? ; Place to hold di register
- Hold_ax DW ? ; Place to hold ax register
- stflg db 0 ; Says if setting SEND or RECEIVE parameter.
- srtmp db 0
- Force_card db 0FFh ; Flag that we are not forcing the card
- savsp dw 0
- temp dw 0
- temp1 dw ? ; Temporary storage.
- temp2 dw ? ; Temporary storage.
-
- b03st db 'BAUD rate is 300$'
- b12st db 'BAUD rate is 1200$'
- b18st db 'BAUD rate is 1800$'
- b24st db 'BAUD rate is 2400$'
- b48st db 'BAUD rate is 4800$'
- b96st db 'BAUD rate is 9600$'
- b04st db 'BAUD rate is 45.5$'
- b05st db 'BAUD rate is 50$'
- b07st db 'BAUD rate is 75$'
- b11st db 'BAUD rate is 110$'
- b13st db 'BAUD rate is 134.5$'
- b15st db 'BAUD rate is 150$'
- b06st db 'BAUD rate is 600$'
- b20st db 'BAUD rate is 2000$'
- b19st db 'BAUD rate is 19200$'
- b23st db 'BAUD rate is 23040$'
- b38st db 'BAUD rate is 38400$'
-
- parmsg db 'PARITY is $'
- locst db 'LOCAL-ECHO is $'
- belon db 'Ring BELL after transfer$'
- beloff db 'No BELL after transfer$'
- Take_echo_is DB 'TAKE-ECHO is $'
- cm1st db 'Communications PORT: 1$'
- cm2st db 'Communications PORT: 2$'
- capmsg db 'LOG is $'
- eofmsg db 'EOF mode is $'
- flost db 'No FLOW-CONTROL used$'
- floxmsg db 'FLOW-CONTROL is XON/XOFF $'
- handst db 'HANDSHAKE is $'
- destst db 'File DESTINATION is $'
- diskst db 'DEFAULT-DISK is $'
- blokst db 'BLOCK-CHECK is $'
- Mode_is db 'MODE is $'
- ebyst db '8-bit quoting done only on request$'
- ebvst db '8-bit quoting will be done with: $'
- escmes db 'ESCAPE character is $'
- ;debon db 'DEBUG mode is $'
- flwon db 'WARNING is $'
- timmsg db 'TIMER is $'
- abfdst db 'INCOMPLETE file: DISCARD$'
- abfkst db 'INCOMPLETE file: KEEP$'
- eolst db 'END-OF-LINE character is $'
- m7171st db '7171-MODE is $'
- AutoWrSt db 'AUTOWRAP-MODE is $'
-
- sqcst db 'SEND cntrl char prefix: $'
- rqcst db 'RECEIVE cntrl char prefix: $'
- ssohst db 'SEND start-of-packet char: $'
- rsohst db 'RECEIVE start-of-packet char: $'
- stimst db 'SEND TIMEOUT (seconds): $'
- rtimst db 'RECEIVE TIMEOUT (seconds): $'
- spakst db 'SEND PACKET-LENGTH: $'
- rpakst db 'RECEIVE PACKET-LENGTH: $'
- snpdst db 'SEND # of PAD chars: $'
- rnpdst db 'RECEIVE # of PAD chars: $'
-
- eolhlp db cr,lf,'Decimal number between 0 and 31$'
- eolerr db cr,lf,'Illegal end-of-line character$'
- timerr db cr,lf,'Illegal timeout value$'
- timhlp db cr,lf,'Decimal number between 0 and 94$'
- soherr db cr,lf,'Illegal start-of-packet character$'
- quohlp db cr,lf,'Decimal number between 33 and 126$'
- quoerr db cr,lf,'Illegal control character prefix$'
- pakerr db cr,lf,'Illegal packet length$'
- pakhlp db cr,lf,'Decimal number between 20 and 94$'
- npderr db cr,lf,'Illegal number of pad characters$'
- npdhlp db cr,lf,'Decimal number between 0 and 99$'
- paderr db cr,lf,'Illegal pad character$'
- padhlp db cr,lf,'Decimal number between 0 and 31 or 127$'
- eschlp db cr,lf,'Enter literal value (ex: Cntrl ]) $'
- desterr db cr,lf,'Illegal destination device$'
- dskhlp db cr,lf,'Default disk drive to use, such as A:$'
- dskerr db cr,lf,'Invalid drive specification$'
-
- sethlp db cr,lf,' AUTOWRAP-MODE on/off',tab,tab,'BAUD rate'
- db cr,lf,' BELL on/off',tab,tab,tab,'BLOCK-CHECK-TYPE'
- db cr,lf,' DEBUG on/off',tab,tab,tab,'DEFAULT-DISK'
- db cr,lf,' DESTINATION file/printer',tab,'DISPLAY color/mono'
- db cr,lf,' END-OF-LINE character',tab,tab,'EOF ctrl-z/noctrl-z'
- db cr,lf,' ESCAPE character',tab,tab,'FLOW-CONTROL'
- db cr,lf,' HANDSHAKE',tab,tab,tab,'INCOMPLETE file'
- db cr,lf,' KEY scan code',tab,tab,tab,'LOCAL-ECHO on/off'
- db cr,lf,' MENU-FILE filename',tab,tab,'MODE command/menu'
- db cr,lf,' PARITY type',tab,tab,tab,'PORT com1/com2'
- db cr,lf,' PROMPT string',tab,tab,tab,'RECEIVE parameter'
- db cr,lf,' REMOTE on/off',tab,tab,tab,'SEND parameter'
- db cr,lf,' TAKE-ECHO on/off',tab,tab,'TIMER on/off'
- db cr,lf,' WARNING on/off',tab,tab,tab,'7171-MODE on/off'
- db '$'
-
- settab db 29
- mkeyw '7171-MODE', m71onoff
- mkeyw 'AUTOWRAP-MODE', AutWrpOnOff
- mkeyw 'BAUD',baudst
- mkeyw 'BELL',bellst
- mkeyw 'BLOCK-CHECK-TYPE',blkset
- mkeyw 'CARD',Set_card
- mkeyw 'DEBUG',debst
- mkeyw 'DEFAULT-DISK',dskset
- mkeyw 'DESTINATION',desset
- mkeyw 'DISPLAY',Set_display
- mkeyw 'END-OF-LINE',eolset
- mkeyw 'EOF',seteof
- mkeyw 'ESCAPE',escape
- mkeyw 'FLOW-CONTROL',floset
- mkeyw 'HANDSHAKE',hndset
- mkeyw 'INCOMPLETE',abfset
- mkeyw 'KEY',setkey
- mkeyw 'LOCAL-ECHO',lcal
- mkeyw 'MENU-FILE', Set_menu_file
- mkeyw 'MODE', Set_mode
- mkeyw 'PARITY',setpar
- mkeyw 'PORT',comset
- mkeyw 'PROMPT',promset
- mkeyw 'RECEIVE',recset
- mkeyw 'REMOTE',remset
- mkeyw 'SEND',sendset
- mkeyw 'TAKE-ECHO',takset
- mkeyw 'TIMER',timset
- mkeyw 'WARNING',filwar
-
-
- seoftab db 2
- mkeyw 'CTRL-Z',1
- mkeyw 'NOCTRL-Z',0
-
- stsrtb db 06 ; Number of options.
- mkeyw 'PACKET-LENGTH',srpack
- mkeyw 'PADCHAR',srpad
- mkeyw 'PADDING',srnpd
- mkeyw 'QUOTE',srquo
- mkeyw 'START-OF-PACKET',srsoh
- mkeyw 'TIMEOUT',srtim
-
- ontab db 02H ; Two entries.
- mkeyw 'OFF',00H
- mkeyw 'ON',01H
-
- destab db 02H ; Two choices.
- mkeyw 'DISK',01H
- mkeyw 'PRINTER',00H
-
- ; What type of block check to use.
- blktab db 03H
- mkeyw '1-CHARACTER-CHECKSUM',1
- mkeyw '2-CHARACTER-CHECKSUM',2
- mkeyw '3-CHARACTER-CRC-CCITT',3
-
- ; If abort when receiving files, can keep what we have or discard. [20d]
-
- abftab db 02H ; Only two options.
- mkeyw 'DISCARD',01H
- mkeyw 'KEEP',00H
-
- Mode_table DB 2
- mkeyw 'COMMAND', 0
- mkeyw 'MENU', 0FFh
-
- partab db 05H ; Five entries. [10 start]
- mkeyw 'EVEN',PAREVN
- mkeyw 'MARK',PARMRK
- mkeyw 'NONE',PARNON
- mkeyw 'ODD',PARODD
- mkeyw 'SPACE',PARSPC
-
- flotab db 2
- mkeyw 'NONE',flonon
- mkeyw 'XON/XOFF',floxon
-
- hndtab db 7
- mkeyw 'BELL',bell
- mkeyw 'CR',cr
- mkeyw 'ESC',esc
- mkeyw 'LF',lf
- mkeyw 'NONE',0
- mkeyw 'XOFF',xoff
- mkeyw 'XON',xon
-
- BStab db 02H ;Two entries [19c start]
- mkeyw 'BACKSPACE',00H
- mkeyw 'DELETE',01H
-
- bdtab db 17
- mkeyw '110',b0110
- mkeyw '1200',b1200
- mkeyw '134.5',b01345
- mkeyw '150',b0150
- mkeyw '1800',b1800
- mkeyw '19200',b19200
- mkeyw '2000',b2000
- mkeyw '23040',b23040
- mkeyw '2400',b2400
- mkeyw '300',b0300
- mkeyw '38400',b38400
- mkeyw '45.5',b00455
- mkeyw '4800',b4800
- mkeyw '50',b0050
- mkeyw '600',b0600
- mkeyw '75',b0075
- mkeyw '9600',b9600
-
- Display_tab db 2
- mkeyw 'COLOR', 0
- mkeyw 'MONOCHROME', 1
-
- Card_tab db 4
- mkeyw 'COLOR', 1
- mkeyw 'DEFAULT', 0FFh
- mkeyw 'EGA', 2
- mkeyw 'MONOCHROME', 0
-
-
- ten dw 10 ; multiplier for setatoi
- rdbuf db 80H DUP(?)
- prm db 30 dup(0) ; Buffer for new prompt.
- prmptr dw kerm ; pointer to prompt
- m7171 db 0 ; in 7171 mode
- AutoWrap db 0 ; In AutoWrap mode
- defkw db 100 dup (?)
- macnum dw 0 ; one macro yet
- mactab dw Exitmac ; default Exit mac is macro 0
- dw macmax dup (?) ; empty macro table
- defptr dw macbuf
- macbuf db macmax*100 dup (?) ; buffer for macro defs
- rmlft db setextra ; space left in set table
- mcctab db 1 ; macro cmd table, one initially
- mkeyw 'EXIT',0 ; macro # 0
- db setextra dup (?) ; room for more.
-
- Exitmac DB imlen-1
- DB 'Drop-Dtr',Cr,'Exit',Cr
- imlen equ $-Exitmac
-
- ; structure for status information
- stent struc
- sttyp dw ? ; type (actually routine to call)
- msg dw ? ; message to print
- val2 dw ? ; needed value: another message, or tbl addr
- tstcel dw ? ; address of cell to test, in data segment
- basval dw 0 ; base value, if non-zero
- stent ends
-
- ; stent <onoff,vtemst,,flags.vtflg>
-
- sttab stent <baudprt>
- stent <srchkw,parmsg,partab,parflg,portval>
- stent <msg2,cm2st,cm1st,flags.comflg>
- stent <onechr,escmes,,trans.escchr>
- stent <onoff,locst,,ecoflg,portval>
- stent <onoff,capmsg,,flags.capflg>
- stent <msg2,flost,floxmsg,floflg,portval>
- stent <prhnd>
- stent <srchkw,destst,destab,flags.destflg>
- stent <drnum,diskst,,curdsk>
- stent <onoff,flwon,,flags.flwflg>
- stent <msg2,beloff,belon,flags.belflg>
- stent <srchkw,eofmsg,seoftab,flags.eofcz>
- stent <msg2,abfkst,abfdst,flags.abfflg>
- stent <onoff,timmsg,,flags.timflg>
- stent <onoff,Take_echo_is,,flags.takflg>
- stent <pr8bit>
- stent <onechr,eolst,,trans.seol>
- stent <onoff,m7171st,,m7171>
- stent <Display,Disp_msg,,Force_mono>
- stent <srchkw,blokst,blktab,trans.chklen>
- stent <onoff,AutoWrSt,,AutoWrap>
-
- ; File transfer params
- stent <onechr,sqcst,,trans.rquote>
- stent <onechr,rqcst,,trans.squote>
- stent <onechr,ssohst,,trans.ssoh>
- stent <onechr,rsohst,,trans.rsoh>
- stent <stnum,stimst,,trans.stime>
- stent <stnum,rtimst,,trans.rtime>
- stent <stnum,spakst,,trans.spsiz>
- stent <stnum,rpakst,,trans.rpsiz>
- stent <stnum,snpdst,,trans.spad>
- stent <stnum,rnpdst,,trans.rpad>
-
- stent <SrchKw,Mode_is,Mode_table,In_menu_mode>
-
- ; stent <onoff,debon,,flags.debug>
- dw 0 ; end of table
- sttbuf db 2000 dup (?) ; big buffer for status msg.
- datas ends
-
- code segment public
- extrn cmcfrm:near, prserr:near, comnd:near, dobaud:near
- extrn cmgtch:near, repars:near, coms:near, defkey:near
- extrn inicpt:near, prompt:near, nout:near, prtscr:near
- extrn prkey:near, serrst:NEAR, serini:NEAR, SPath:NEAR
- EXTRN Parse_for_Set_Key:NEAR, Get_Set_Key_table_size:NEAR
- assume cs:code,ds:datas
-
- ; This is the SET command.
-
- SETCOM PROC NEAR
- mov dx,offset settab ; Parse a keyword from the set table.
- mov bx,offset sethlp
- mov ah,cmkey
- call comnd
- jmp r
- jmp bx ; Run the routine
- SETCOM endp
-
- docom proc near
- mov dx,offset mcctab
- mov bx,0
- mov ah,cmkey
- call comnd
- jmp r
- push bx
- mov ah,cmcfm
- call comnd
- pop bx
- ret
- nop
- pop bx
- cmp taklev,maxtak ; room in take level?
- jl docom2 ; yes, continue
- mov dx,offset ermes4 ; else complain
- jmp reterr
- docom2: inc taklev ; increment take level (overflow)
- add takadr,size takinfo
- shl bx,1
- mov si,mactab[bx] ; point to macro
- mov cl,[si] ; get size from macro
- mov ch,0
- inc si ; point to actual definition
- mov bx,takadr ; point to current buffer
- mov [bx].takfcb,0ffh ; flag as a macro
- mov [bx].takptr,si ; point to beginning of def
- mov [bx].takchl,cl ; # of chars left in buffer
- mov [bx].takcnt,cx ; and in definition
- mov word ptr [bx].takcnt+2,0 ; zero high order...
- jmp rskp
- docom endp
-
- ; the define command
- dodef proc near
- cmp macnum,macmax ; get current macro count
- jl dode1 ; no, go on
- mov dx,offset ermes1 ; else complain
- jmp reterr ; and return
-
- dode1: mov ah,cmtxt
- mov bx,offset defkw+1 ; buffer for keyword
- mov dx,offset macmsg
- call comnd
- ret
- nop
- nop
- cmp ah,0
- jne dode2
- jmp RSkp
- dode2: push es
- mov bx,ds
- mov es,bx
- cld
- mov cl,ah
- mov ch,0 ; length
- mov si,offset defkw+1 ; pointer to keyword
- mov ah,0 ; # of chars in keyword
- ; uppercase keyword, look for end
- dode3: lodsb ; get a byte
- cmp al,'a'
- jb dode4
- cmp al,'z'
- ja dode4
- sub al,'a'-'A'
- mov [si-1],al ; uppercase if necessary
- dode4: inc ah ; increment word count
- cmp al,' ' ; is it the break character?
- loopne dode3 ; no, loop thru rest of word
- dode5: jne dode6 ; ended with break char?
- dec ah ; yes, don't count in length
- dode6: mov defkw,ah ; store length in front of it
- add ah,4 ; add keyword overhead length
- cmp ah,rmlft ; will it fit in buffer
- jb dode7 ; yes, keep going
- mov dx,offset ermes2 ; else complain
- jmp reterr
-
- dode7: sub rmlft,ah ; subtract space used in tbl
- mov di,defptr ; pointer to free space
- inc macnum ; count the macro
- mov bx,macnum
- shl bx,1 ; double for word idx!!!
- mov mactab[bx],di ; install into table
- mov [di],cl ; store length
- inc di
- jcxz dode10 ; no copy if 0 length
-
- ; copy definition into buffer, changing commas to crs
- dode8: lodsb ; get a byte
- cmp al,',' ; comma?
- jne dode9 ; no, keep going
- mov al,cr ; else replace with cr
- dode9: stosb
- loop dode8 ; keep copying
-
- dode10: mov defptr,di ; update free ptr
- mov bl,defkw
- mov bh,0
- lea di,defkw+1[bx] ; end of keyword
- mov al,'$'
- stosb
- mov ax,macnum
- stosb ; low-order
- mov al,0 ; high-order is always 0.
- stosb
-
- ; now install into table
- pop es
- mov bx,offset mcctab
- mov dx,offset defkw
- call addtab
- jmp rskp
- dodef endp
-
- ; add an entry to a keyword table
- ; enter with bx/ table address, dx/ ptr to new entry
- ; no check is made to see if the entry fits in the table.
- addtab PROC NEAR
- push es
- cld
- mov ax,ds
- mov es,ax ; address data segment
- mov bp,bx ; remember where tbl starts
- mov cl,[bx] ; pick up length of table
- mov ch,0
- inc bx ; point to actual table...
- addta1: push cx ; preserve count
- mov si,dx ; point to entry
- lodsb ; get length of new entry
- mov cl,[bx] ; and length of table entry...
- mov ah,0 ; assume they're the same size
- cmp al,cl ; are they the same?
- lahf ; remember result of comparison...
- jae addta2 ; is new smaller? no, use table length
- mov cl,al ; else use length of new entry
- addta2: mov ch,0
- lea di,[bx+1] ; point to actual keyword
- repe cmpsb ; compare strings
- pop cx ; restore count
- jb addta4 ; below, insert before this one
- jne addta3 ; not below or same, keep going
- sahf ; same. get back result of length comparison
- jb addta4 ; if new len is smaller, insert here
- jne addta3 ; if not same size, keep going
- mov si,bx ; else this is where entry goes
- jmp short addta6 ; no insertion required...
- addta3: mov al,[bx]
- mov ah,0
- add bx,ax ; skip this entry
- add bx,4 ; len + $ + value...
- loop addta1 ; and keep looking
- addta4: mov si,bx ; this is first location to move
- mov di,bx
- inc ds:byte ptr [bp] ; remember we're adding one...
- jcxz addta6 ; no more entries, forget this stuff
- mov bh,0 ; this stays 0
- addta5: mov bl,[di] ; get length
- lea di,[bx+di+4] ; end is origin + length + 4 for len, $, value
- loop addta5 ; loop thru remaining keywords
- mov cx,di
- sub cx,si ; compute # of bytes to move
- push si ; preserve loc for new entry
- mov si,di ; first to move is last
- dec si ; minus one
- mov di,dx ; new entry
- mov bl,[di] ; get length
- lea di,[bx+si+4] ; dest is source + length of new + 4
- std ; move backwards
- rep movsb ; move the table down
- cld ; put flag back
- pop si
- addta6: mov di,si ; this is where new entry goes
- mov si,dx ; this is where it comes from
- mov cl,[si] ; length
- mov ch,0
- add cx,4 ; overhead bytes
- rep movsb ; stick it in
- pop es
- ret ; and return
- addtab endp
-
- ; Show defined macros.
- SHOMAC PROC NEAR
- mov ah,cmtxt
- mov bx,offset rdbuf
- mov dx,offset shmmsg
- call comnd
- jmp r
- cmp ah,0 ; Bare CR means show all macros.
- jne shom2 ; No, he wants specific macro expanded.
- mov si,offset mcctab ; Table of macro names.
- lodsb
- mov cl,al ; Number of macro entries.
- mov ch,0
- jcxz shom1 ; Done if none left to display.
-
- shom0: lodsb ; Length of macro name.
- push ax ; Don't forget it.
-
- mov ah,prstr
- mov dx, OFFSET Blank ; Indent by one space
- int dos
-
- mov dx,si ; Print macro name.
- int dos
- mov dx,offset eqs
- int dos
- pop ax
- mov ah,0
- add si,ax ; Skip over name.
- inc si ; Get to macro number.
- mov bx,[si] ; Pick it up.
- call expmac ; Expand the macro.
- add si,2 ; Skip over macro number.
-
- mov ah, PrStr
- mov dx, OFFSET CrLf
- int Dos
-
- loop shom0 ; Do more if any
-
- shom1: jmp rskp
-
- shom2: mov ah,prstr
- mov dx,offset ermes3
- int Dos
-
- jmp rskp
-
- SHOMAC ENDP
-
- ; Expand the macro, called with BX/macro number.
- expmac: push si
- push cx
- mov si,offset mactab ; Table of address expansions.
- shl bx,1 ; Double and use as index into table.
- mov si,[si+bx] ; Get address of expansion in question.
- mov ax,si ; Address of string.
- inc ax ; Don't print length.
- mov cl,[si] ; Length of string.
- mov ch,0
- call prkey ; Print it.
- pop cx
- pop si
- ret
-
- seteof proc near
- mov ah,cmkey
- mov bx,0
- mov dx,offset seoftab
- call comnd
- jmp r
- push bx
- mov ah,cmcfm
- call comnd
- jmp seteo1 ; error return...
- nop
- pop bx
- mov flags.eofcz,bl ; set value
- jmp rskp ; and return
- seteo1: pop bx
- ret
- seteof endp
-
- ; This is the ESCAPE character SET subcommand. [6 start]
-
- ESCAPE PROC NEAR
- call cmgtch ; Get a char.
- cmp ah,0
- jns es1 ; Terminator or no?
- and ah,7FH ; Turn off minus bit.
- cmp ah,'?'
- jne es0
- mov dx,offset eschlp
- mov ah,prstr
- int dos
- mov dx,offset crlf
- int dos
- mov dx,comand.cmprmp
- int dos
- mov bx,comand.cmdptr
- mov al,'$'
- mov [bx],al
- mov dx,offset comand.cmdbuf
- int dos
- dec comand.cmcptr ; Ignore dollar sign.
- dec comand.cmccnt
- mov comand.cmaflg,0
- jmp repars
- es0: mov ah,prstr
- mov dx,offset ermes3
- int dos
- jmp RSkp
- es1: mov temp,ax
- call cmcfrm
- jmp es0
- nop ; Take up 3 bytes.
- mov ax,temp
- mov trans.escchr,ah ; Save new value.
- jmp RSkp
- ESCAPE ENDP ; [6 end]
-
- ; This is the End-of-line character SET subcommand.
-
- EOLSET PROC NEAR
- mov min,0
- mov max,1FH
- mov sum,0
- mov tmp,10
- mov temp1,0
- mov desta,offset trans.seol
- mov numhlp,offset eolhlp
- mov numerr,offset eolerr
- jmp num0 ; Common routine for parsing numerical input.
- EOLSET ENDP
-
- num0: call cmgtch ; Get the first char into AH.
- cmp ah,0
- js num1
- cmp ah,'0'
- jl num1
- cmp ah,'9'
- ja num1
- mov temp1,1
- sub ah,30H
- mov dl,ah
- mov al,sum
- mul tmp
- add al,dl
- mov sum,al
- jmp num0
- num1: and ah,7FH
- cmp ah,CR
- jne num2
- cmp temp1,0
- je num21
- mov al,sum
- cmp al,min
- jl num3
- cmp al,max
- jg num3
- mov bx,desta
- mov [bx],al
- ret
- num2: cmp ah,03FH ; Question mark?
- je num4
- num21: mov ah,prstr
- mov dx,offset ermes3
- int dos
- jmp prserr
- num3: mov ah,prstr
- mov dx,numerr
- int dos
- jmp prserr
- num4: mov ah,prstr
- mov dx,numhlp
- int dos
- mov dx,offset crlf
- int dos
- mov dx,comand.cmprmp
- int dos
- mov bx,comand.cmdptr
- mov al,'$'
- mov [bx],al
- mov dx,offset comand.cmdbuf
- int dos
- dec comand.cmcptr ; Don't count the dollar sign.
- dec comand.cmccnt ; Or the question mark.
- mov comand.cmaflg,0 ; Check for more input.
- jmp repars
-
- ; This is the LOCAL echo SET subcommand.
-
- LCAL PROC NEAR
- mov dx,offset ontab
- mov bx,0
- mov ah,cmkey
- call comnd
- jmp r
- push bx ; Save the parsed value.
- mov ah,cmcfm
- call comnd ; Get a confirm.
- jmp lcl0 ; Didn't get a confirm.
- nop
- pop bx
- mov si,portval
- mov [si].ecoflg,bl ; Set the local echo flag.
- ;tm mov [si].hndflg,bl ; This goes on/off with local echo.
- xor bl,01 ; Toggle this.
- ;tm mov [si].floflg,bl ; This is the opposite.
- jmp RSkp
- lcl0: pop bx
- ret
- LCAL ENDP
-
- ; This is the SET subcommand to choose between COM1 and COM2. [19b]
-
- COMSET PROC NEAR
- call serrst ; Reset the old port, if any, uninstalling
- ; interrupt handler
- call coms ; Switch to the desired port (may be same)
- call serini ; Then turn on the port and install interrupt
- ; handler
- jmp RSkp ; Return to command loop
- COMSET ENDP
-
- FILWAR PROC NEAR
- mov dx,offset ontab
- mov bx,0
- mov ah,cmkey
- call comnd
- jmp r
- push bx
- mov ah,cmcfm
- call comnd ; Get a confirm.
- jmp fil0 ; Didn't get a confirm.
- nop
- pop bx
- mov flags.flwflg,bl ; Set the filewarning flag.
- jmp RSkp
- fil0: pop bx
- ret
- FILWAR ENDP
-
-
- ; Turn on or off the setting of 7171 mode
-
- m71onoff PROC
-
- mov dx,offset ontab
- mov bx,0
- mov ah,cmkey
- call comnd
- jmp r
- push bx
- mov ah,cmcfm
- call comnd ; Get a confirm
- jmp m7x ; Didn't get a confirm
- nop
- pop bx
- mov m7171,bl ; Store the new setting
- jmp RSkp
- m7x: pop bx
- ret
-
- m71onoff ENDP
-
- ; Turn on or off the setting of AutoWrap mode
-
- AutWrpOnOff PROC
-
- mov dx,offset ontab
- mov bx,0
- mov ah,cmkey
- call comnd
- jmp r
- push bx
- mov ah,cmcfm
- call comnd ; Get a confirm
- jmp AuWrx ; Didn't get a confirm
- nop
- pop bx
- mov AutoWrap, bl ; Store the new setting
- jmp RSkp
- AuWrx: pop bx
- ret
-
- AutWrpOnOff ENDP
-
- ; This is the SET aborted-file command. [20d]
-
- ABFSET PROC NEAR
- mov dx,offset abftab
- mov bx,0
- mov ah,cmkey
- call comnd
- jmp r
- push bx
- mov ah,cmcfm
- call comnd ; Get a confirm.
- jmp abf0 ; Didn't get a confirm.
- nop
- pop bx
- mov flags.abfflg,bl ; Set the aborted file flag.
- jmp RSkp
- abf0: pop bx
- ret
- ABFSET ENDP
-
- %OUT >> About half way through source file
-
- ; This is the SET Parity command. [10 start]
-
- SETPAR PROC NEAR
- mov dx,offset partab
- mov bx,0
- mov ah,cmkey
- call comnd
- jmp r
-
- mov Hold_bx, bx
- mov ah,cmcfm
- call comnd ; Get a confirm.
- jmp R
-
- mov bx, Hold_bx
-
- mov si,portval
- mov [si].parflg,bl ; Set the parity flag.
- cmp bl,parnon ; Resetting parity to none? [21b]
- je setp0 ; Yes, reset 8 bit quote character. [21b]
- mov trans.ebquot,dqbin ; Else, do quoting. [21b]
- jmp RSkp ; That's it. [21b]
- setp0: mov trans.ebquot,'Y' ; If none, say will quote upon request. [21b]
- jmp RSkp
- par0: pop bx
- ret
- SETPAR ENDP ; [10 end]
-
-
- ; SET MENU-FILE command -- sets name of next MENU file
-
- Set_Menu_file PROC
-
- cld ; Forwards
- cmp TakLev, MaxTak ; Hit our limit?
- jl SMF_1 ; Continue if still OK
-
- mov ah, PrStr
- mov dx, OFFSET ErMs38 ; Complain
- int Dos
-
- jmp RSkp
-
- SMF_1: mov di, TakAdr
- add di, SIZE TakInfo
- mov Hold_di, di ; Save reg
-
- mov ah, CmTxt
- lea bx, [di].TakBuf ; Convenient place to parse name into
- mov dx, OFFSET FilMsg ; Help in case user types "?"
- call comnd ; Parse for a text string
- jmp RSkp ; Can't get text string (?), give up
-
- mov di, Hold_di ; Restore reg
- lea si, [di].TakBuf ; Get buffer back
- mov bl, ah ; Length of thing parsed
- sub bh, bh ; Zero top half
- mov BYTE PTR [bx+si], 0 ; Make it ASCIZ
- mov Hold_ax, ax ; Save ax for a moment
- mov ax, si ; Point to name again
- call SPath ; Is it around?
- jc SMF_2 ; No, go complain
-
- mov di, Hold_di ; Restore reg
- lea si, [di].TakBuf ; Get buffer back
- mov di, OFFSET Menu_file_name ; Ptr to where menu file name is stored
- mov cl, BYTE PTR Hold_ax + 1 ; Pick up count
- sub ch, ch ; Clear high half
- rep movsb ; Copy menu file name
-
- mov Reload_menu_flag, 1 ; Flag that we need to reload the menu file
- jmp RSkp ; Done here
-
-
- SMF_2: mov ah,prstr
- mov dx,offset erms31
- int dos
- jmp RSkp
-
- Set_Menu_file ENDP
-
-
- ; SET MODE command -- sets COMMAND or MENU mode
-
- Set_Mode PROC
-
- mov dx, OFFSET Mode_table
- mov bx, 0
- mov ah, cmkey
- call comnd
- jmp RSkp
-
- mov Hold_bx, bx
- mov ah, CmCfm
- call Comnd ; Get a confirm
- jmp R ; Didn't get a confirm
-
- mov bx, Hold_bx
- mov In_menu_mode, bl ; Store the flag
-
- jmp RSkp
-
- Set_Mode ENDP
-
-
- ; Sets debugging mode on and off.
-
- DEBST PROC NEAR
- mov dx,offset ontab
- mov bx,0
- mov ah,cmkey
- call comnd
- jmp r
- push bx
- mov ah,cmcfm
- call comnd ; Get a confirm.
- jmp deb0 ; Didn't get a confirm.
- nop
- pop bx
- mov flags.debug,bl ; Set the DEBUG flag.
- jmp RSkp
- deb0: pop bx
- ret
- DEBST ENDP
-
- ; Turn bell on or off. [17a start]
-
- BELLST PROC NEAR
- mov dx,offset ontab
- mov bx,0
- mov ah,cmkey
- call comnd
- jmp r
- push bx
- mov ah,cmcfm
- call comnd
- jmp bel0
- nop
- pop bx
- mov flags.belflg,bl
- jmp RSkp
- bel0: pop bx
- ret
- BELLST ENDP ; [17a end]
-
- ; Toggle echo'ing of TAKE file to be either ON or OFF.
- TAKSET PROC NEAR
- mov dx,offset ontab
- mov bx,0
- mov ah,cmkey
- call comnd
- jmp r
- push bx
- mov ah,cmcfm
- call comnd
- jmp tak0
- nop
- pop bx
- mov flags.takflg,bl
- jmp RSkp
- tak0: pop bx
- ret
- TAKSET ENDP ; [17a end]
-
- ; Set timer ON/OFF during file transfer.
- TIMSET PROC NEAR
- mov dx,offset ontab
- mov bx,0
- mov ah,cmkey
- call comnd
- jmp r
- push bx
- mov ah,cmcfm
- call comnd
- jmp tim0
- nop
- pop bx
- mov flags.timflg,bl
- jmp RSkp
- tim0: pop bx
- ret
- TIMSET ENDP ; [17a end]
-
- ; Allow user to change the "Kermit-MS>" prompt.
- PROMSET PROC NEAR
- mov ah,cmtxt
- mov bx,offset prm ; Read in the prompt.
- mov dx,offset prmmsg
- call comnd
- jmp r
- cmp ah,0 ; Just a bare CR?
- jne prom0
- mov ax,offset kerm
- jmp prom1
- prom0: mov byte ptr [bx],'$' ; End of string.
- mov ax,offset prm
- prom1: mov prmptr,ax ; Remember it.
- jmp rskp
- PROMSET ENDP
-
- ; Set Flow-Control subcommand.
- FLOSET PROC NEAR
- mov dx,offset flotab
- xor bx,bx
- mov ah,cmkey
- call comnd
- jmp r
- push bx
- mov ah,cmcfm
- call comnd ; Get a confirm.
- jmp flox ; Didn't get a confirm.
- nop
- pop bx
- mov si,portval
- mov [si].flowc,bx ; Flow control value.
- cmp bx,0 ; Turning it off?
- je flo0 ; Yes.
- mov [si].floflg,1 ; Say we're doing flow control.
- mov [si].hndflg,0 ; So don't do handshaking.
- jmp RSkp
- flo0: mov [si].floflg,bl ; Say we're not doing flow control.
- jmp RSkp
- flox: pop bx
- ret
- FLOSET ENDP
-
- ; Set Handshake subcommand.
- HNDSET PROC NEAR
- mov dx,offset hndtab
- mov bx,0
- mov ah,cmkey
- call comnd
- jmp r
- push bx
- mov ah,cmcfm
- call comnd ; Get a confirm.
- jmp hndx ; Didn't get a confirm.
- nop
- pop bx
- mov si,portval
- cmp bl,0 ; Setting handshake off?
- je hnd0 ; Yes.
- mov [si].floflg,0 ; Else, turn flow control off.
- mov [si].hndflg,1 ; And turn on handshaking.
- mov [si].hands,bl ; Use this char as the handshake.
- jmp RSkp
- hnd0: mov [si].hndflg,0 ; No handshaking.
- mov [si].floflg,1 ; If one is off, the other is on.
- jmp RSkp
- hndx: pop bx
- ret
- HNDSET ENDP
-
- ; Set block check type sub-command.
- BLKSET PROC NEAR
- mov dx,offset blktab
- mov bx,0
- mov ah,cmkey
- call comnd
- jmp r
- push bx
- mov ah,cmcfm
- call comnd ; Get a confirm.
- jmp blk0 ; Didn't get a confirm.
- nop
- pop bx
- mov trans.chklen,bl ; Use this char as the handshake.
- mov inichk,bl ; Save here too.
- jmp RSkp
- blk0: pop bx
- ret
- BLKSET ENDP
-
- ; Set destination for incoming file.
- DESSET PROC NEAR
- mov dx,offset destab
- mov bx,0
- mov ah,cmkey
- call comnd
- jmp r
- push bx
- mov ah,cmcfm
- call comnd ; Get a confirm.
- jmp des0 ; Didn't get a confirm.
- nop
- pop bx
- mov flags.destflg,bl ; Set the destination flag.
- jmp RSkp
- des0: pop bx
- ret
- DESSET ENDP
-
- ; Set default disk for sending/receiving, etc.
- DSKSET PROC NEAR
- mov comand.cmcr,1 ; Don't want filename specified.
- mov ah,cmifi ; Parse for drive specification.
- mov dx,offset rdbuf ; Read into handy buffer.
- mov bx,offset dskhlp ; Text of help message.
- call comnd
- jmp r
- mov ah,cmcfm
- call comnd
- jmp r
- cmp flags.nmoflg,0 ; Fail if specified file name.
- je dsk1
- dsk0: mov ah,prstr
- mov dx,offset dskerr ; Illegal drive specification.
- int dos
- jmp RSkp
- dsk1: mov bx,offset rdbuf
- mov ah,[bx] ; Get the drive they said to use.
- cmp ah,0 ; Did they type a bare CR?
- je dsk0 ; Yes, complain.
- mov curdsk,ah ; And remember it.
-
- ; Don't actually switch disks, just remember where sent/received files go
-
- ; dec ah
- ; mov dl,ah
- ; mov ah,seldsk
- ; int dos
-
- ; Oh well, for now ...
-
- dec ah
- mov dl,ah
- mov ah,seldsk
- int dos
-
- jmp RSkp
-
- DSKSET ENDP
-
- ; This function sets the baud rate.
-
- BAUDST PROC NEAR
- mov dx,offset bdtab
- mov bx,0
- mov ah,cmkey
- call comnd
- jmp r
- push bx
- mov ah,cmcfm
- call comnd ; Get a confirm.
- jmp bau0 ; Didn't get one.
- nop
- pop bx
- mov si,portval
- mov ax,[si].baud ; Remember original value. [25]
- mov [si].baud,bx ; Set the baud rate.
- call dobaud ; Use common code. [19a]
- jmp RSkp
- bau0: pop bx
- ret
- BAUDST ENDP
-
- SENDSET PROC NEAR
- mov stflg,'S' ; Setting SEND parameter
- sndst0: mov dx,offset stsrtb ; Parse a keyword.
- mov bx,0
- mov ah,cmkey
- call comnd
- jmp r
- call bx
- nop
- nop
- nop
- jmp rskp
- SENDSET ENDP
-
- recset: mov stflg,'R' ; Setting RECEIVE paramter.
- jmp sndst0
-
- remset proc near
- mov ah,cmkey
- mov dx,offset ontab
- mov bx,0
- call comnd
- jmp r
- push bx ; save parsed value
- mov ah,cmcfm
- call comnd ; confirm
- pop bx
- ret ; return on failure
- nop
- pop bx
- mov flags.remflg,bl ; set remote setting
- mov flags.Real_RemFlg,bl ; Set "real" remote setting
- jmp rskp ; and return
- remset endp
-
- ; Set send/receive start-of-header.
- srsoh: mov min,0
- mov max,1FH
- mov sum,0
- mov tmp,10
- mov desta,offset trans.ssoh ; Assume SEND.
- cmp stflg,'S' ; Setting SEND paramter?
- je srsoh0
- mov desta,offset trans.rsoh
- srsoh0: mov numhlp,offset eolhlp ; Reuse help message.
- mov numerr,offset soherr
- mov temp1,0
- jmp num0 ; Common routine for parsing numerical input.
-
- ; Set send/receive timeout.
- srtim: mov min,0
- mov max,94
- mov sum,0
- mov tmp,10
- mov desta,offset trans.stime ; Assume SEND.
- cmp stflg,'S' ; Setting SEND paramter?
- je srtim0
- mov desta,offset trans.rtime
- srtim0: mov numhlp,offset timhlp ; Reuse help message.
- mov numerr,offset timerr
- mov temp1,0
- jmp num0 ; Common routine for parsing numerical input.
-
- ; Set send/receive packet length.
- srpack: mov min,20
- mov max,94
- mov sum,0
- mov tmp,10
- mov desta,offset trans.spsiz
- cmp stflg,'S' ; Setting SEND paramter?
- je srpak0
- mov desta,offset trans.rpsiz
- srpak0: mov numhlp,offset pakhlp
- mov numerr,offset pakerr
- mov temp1,0
- jmp num0 ; Parse numerical input.
-
- ; Set send/receive number of padding characters.
- srnpd: mov min,0
- mov max,99
- mov sum,0
- mov tmp,10
- mov desta,offset trans.spad
- cmp stflg,'S' ; Setting SEND paramter?
- je srnpd0
- mov desta,offset trans.rpad
- srnpd0: mov numhlp,offset npdhlp
- mov numerr,offset npderr
- mov temp1,0
- jmp num0 ; Parse numerical input.
-
- ; Set send/receive padding character.
- srpad: mov min,0
- mov max,127
- mov sum,0
- mov tmp,10
- mov srtmp,0FFH ; Haven't seen anything yet.
- mov desta,offset srtmp
- mov numhlp,offset padhlp
- mov numerr,offset paderr
- mov temp1,0
- mov savsp,sp
- call num0 ; Parse numerical input.
- mov sp,savsp
- mov temp,offset trans.spadch
- cmp stflg,'S'
- je srpad1
- mov temp,offset trans.rpadch
- srpad1: mov bx,offset srtmp
- mov ah,[bx]
- cmp ah,0FFH ; Did they end up not doing the command?
- je srpad3
- cmp ah,127 ; This is allowed.
- je srpad2
- cmp ah,32
- jb srpad2 ; Between 0 and 31 is OK too.
- mov ah,prstr
- mov dx,offset paderr
- int dos
- jmp RSkp
- srpad2: mov bx,temp ; Set the real pad char.
- mov [bx],ah
- srpad3: jmp RSkp
-
- ; Set send/receive control character prefix.
- srquo: mov min,33
- mov max,126
- mov sum,0
- mov tmp,10
- mov desta,offset trans.rquote ; Used for outgoing packets.
- cmp stflg,'S' ; Setting outgoing quote char?
- je srquo0
- mov desta,offset trans.squote ; For incoming quote char.
- srquo0: mov numhlp,offset quohlp
- mov numerr,offset quoerr
- mov temp1,0
- jmp num0 ; Parse numerical input.
-
-
- ; Set Card Monochrome, Color or EGA
-
- Set_card PROC
-
- mov dx, OFFSET Card_tab
- mov bx,0
- mov ah,cmkey
- call comnd
- jmp r
- push bx
- mov ah,cmcfm
- call comnd ; Get a confirm
- jmp SC_ret ; Didn't get a confirm
- nop
-
- mov Force_card, bl ; Save the value we got
- pop bx
- jmp RSkp
-
- SC_ret: pop bx
- ret
-
- Set_card ENDP
-
-
- ; Set Display Color or Monochrome
-
- Set_Display PROC
-
- mov dx, OFFSET Display_tab
- mov bx,0
- mov ah,cmkey
- call comnd
- jmp r
- push bx
- mov ah,cmcfm
- call comnd ; Get a confirm
- jmp SD_ret ; Didn't get a confirm
- nop
-
- mov Force_mono, bl ; Save the value we got
- pop bx
- jmp RSkp
-
- SD_ret: pop bx
- ret
-
- Set_Display ENDP
-
-
- ; This is the STATUS command.
-
- STATUS PROC NEAR
- mov ah,cmcfm
- call comnd ; Get a confirm.
- jmp r ; Didn't get a confirm.
- call stat0
- mov cx,di ; End of buffer
- sub cx,ax ; Get length of buffer.
- dec cx ; Account for null.
- mov di,ax ; Buffer pointer.
- call prtscr ; Put data onto the screen.
- jmp rskp
- STATUS ENDP
-
- ; Return a pointer to status message in AX, ptr to end in DI.
-
- STAT0 PROC NEAR
- push es
- mov ax,ds
- mov es,ax ; address data segment
- cld ; make sure strings go the right way
- mov di,offset sttbuf ; point to destination buffer
- mov bx,offset sttab ; table to control printing
- mov al,' ' ; start with a space
- stosb ; in the buffer
- mov ax,0 ; need-new-line flag
- stat01: cmp word ptr [bx],0 ; end of table?
- je stat02 ; yes, exit routine
- push bx
- push di ; remember important values
- push ax
- call [bx].sttyp ; call the appropriate routine
- pop ax
- pop cx ; return buffer value
- pop bx ; and ptr
- or ax,ax ; do we need a newline?
- jne stat03 ; yes, go put one in
- sub cx,di ; else see how many columns they used
- add cx,40 ; this is where we'd like to be
- ; if cx is negative here, we have a problem...
- mov al,' '
- rep stosb ; add right # of spaces
- mov ax,1 ; note we need a newline next time
- jmp short stat04 ; and keep looping around
- stat03: mov cx,3
- mov si,offset crlfsp
- rep movsb ; append crlf to string
- xor ax,ax ; reset newline flag
- stat04: add bx,size stent ; advance to next one
- jmp stat01
- stat02: mov al, Cr ; End with an extra CrLf
- stosb
- mov al, Lf
- stosb
- mov al,0 ; end buffer
- stosb
- mov ax,offset sttbuf
- pop es ; restore this
- ret ; and return
- STAT0 ENDP
-
- ; handler routines for status
- ; all are called with di/ destination buffer, bx/ stat ptr. They
- ; can change any register but the segment registers, must update
- ; di to the end of the buffer.
-
- ; copy the message into the buffer
- stmsg proc near
- mov si,[bx].msg ; get message address
- stms1: lodsb ; get a byte
- stosb ; drop it off
- cmp al,'$' ; end of message?
- jne stms1 ; no, keep going
- dec di ; else back up ptr
- ret ; and return
- stmsg endp
-
- ; get address of test value in stent. Returns address in si
- stval proc near
- mov si,[bx].basval ; get base value
- cmp si,0 ; any there?
- je stva1 ; no, keep going
- mov si,[si] ; yes, use as base address
- stva1: add si,[bx].tstcel ; add offset of test cell
- ret ; and return it
- stval endp
-
- ; print a single character
- onechr proc near
- call stmsg ; copy message part first
- call stval ; pick up test value address
- mov al,[si] ; this is char to print
- cmp al,' ' ; printable?
- jae onech1 ; yes, keep going
- add al,64 ; make printable.
- mov byte ptr [di],'^'
- inc di ; note ctrl char
- onech1: stosb ; drop char off
- ret ; and return
- onechr endp
-
- ; numeric field...
- stnum proc near
- call stmsg ; copy message
- call stval ; pick up value address
- mov al,[si] ; get value
- mov ah,0 ; high order is 0
- call outnum ; put number into buffer
- ret ; and return
- stnum endp
-
- ; translate the number in ax...
- outnum proc near
- cwd
- mov bx,10
- div bx ; divide to get digit
- push dx ; save remainder digit
- or ax,ax ; test quotient
- jz outnu1 ; zero, no more of number
- call outnum ; else call for rest of number
- outnu1: pop ax ; get digit back
- add al,'0' ; make printable
- stosb ; drop it off
- ret ; and return
- outnum endp
-
- ; on/off field
- onoff proc near
- call stmsg ; copy message
- call stval ; get value cell
- mov al,[si]
- mov si,offset onmsg
- mov cx,2 ; assume 2-byte 'ON' message
- or al,al ; test value
- jnz onof1 ; on, have right msg
- mov si,offset offmsg
- mov cx,3
- onof1: rep movsb ; copy right message in
- ret ; and return
- onoff endp
-
- ; Display permitted to be Color or forced to be Monochrome
-
- Display PROC
-
- call stmsg ; copy message
- call stval ; get value cell
- mov al,[si]
- mov si,offset Display_color
- mov cx, 21 ; assume Color message
- or al,al ; test value
- jz Disp_1 ; It's COLOR
-
- mov si,offset Display_mono
- mov cx, 23 ; Monochrome message
-
- Disp_1: rep movsb ; Copy right message in
- ret ; and return
-
- Display ENDP
-
-
- ; print first message if false, second if true
- msg2 proc near
- call stval ; get value cell
- mov al,[si]
- mov si,[bx].msg ; assume off
- or al,al ; is it?
- jz msg21 ; yes, continue
- mov si,[bx].val2 ; else use alternate message
- msg21: jmp stms1 ; handle copy and return
- msg2 endp
-
- ; search a keyword table for a value, print that value
- srchkw proc near
- call stmsg ; first print message
- call stval
- mov al,[si] ; get value to hunt for
- mov ah,0 ; high order is 0
- mov bx,[bx].val2 ; this is table address
- jmp prttab ; and look in table.
- srchkw endp
-
- ; Print the drive name.
- drnum proc near
- call stmsg ; copy message part first
- call stval ; pick up test value address
- mov al,[si] ; this is char to print
- add al,'@' ; Make it printable.
- stosb
- mov byte ptr [di],':'
- inc di ; end with a colon
- ret ; and return
- drnum endp
-
- ; print 8-bit quoting
- pr8bit proc near
- mov bl,trans.ebquot ; get quote char
- mov si,offset ebyst ; assume no 8-bit quoting
- cmp bl,'Y' ; on request only?
- je pr8bi1 ; yes, continue
- mov si,offset ebvst ; else variable
- pr8bi1: call stms1 ; copy message in
- cmp bl,'Y' ; not doing it?
- je pr8bi2 ; no, forget this part
- mov [di],bl ; else drop off char too
- inc di
- pr8bi2: ret ; and return
- pr8bit endp
-
- ; Print the handshake.
- prhnd: mov si,offset handst ; copy in initial message
- call stms1
- mov si,offset nonmsg ; assume no handshake
- mov bx,portval
- cmp [bx].hndflg,0 ; Is handshaking in effect?
- jne prh0 ; Yes, print what we're using.
- jmp stms1 ; no, say so and return
- prh0: mov al,'^' ; Doing handshaking with control char.
- stosb
- mov al,[bx].hands
- add al,40H ; Make printable.
- stosb ; put in buffer
- ret ; and return
-
- ; Print the pad character in AL.
- prpad: cmp al,127 ; Are they using a delete?
- jne prpad0
- mov ah,prstr
- mov dx,offset delmsg
- int dos
- ret
- prpad0: mov dl,'^'
- mov ah,conout
- push ax
- int dos
- pop ax
- mov dl,al
- add dl,40H ; Make printable.
- int dos
- ret
-
- ; Print value from table. BX/address of table, AL/value of variable.
- prttab: mov cl,[bx] ; Number of entries in our table.
- inc bx ; Point to the data.
- prtt0: mov dl,[bx] ; Length of keyword.
- inc bx ; Point to keyword.
- mov dh,0
- inc dx ; Account for "$" in table.
- mov si,dx ; Put to index register.
- cmp ax,[bx+si] ; Is this the one?
- je prtt1
- add bx,dx ; Go to end of keyword.
- add bx,2 ; Point to next keyword.
- dec cl ; Any more keywords to check?
- jnz prtt0 ; Yes, go to it.
- mov bx,offset prterr
- prtt1: mov si,bx
- prtt2: jmp stms1 ; copy in message
- ret ; and return
-
- ; This routine prints out the escape character in readable format.
-
- ESCPRT PROC NEAR ; [6 start]
- mov dl,trans.escchr
- cmp dl,' '
- jge escpr2
- push dx
- mov ah,prstr
- mov dx,offset esctl
- int dos
- pop dx
- add dl,040H ; Make it printable.
- escpr2: mov ah,conout
- int dos
- ret
- ESCPRT ENDP ; [6 end]
-
- ; Print information on the baud rate. [19a]
-
- BAUDPRT PROC NEAR
- mov si,portval
- mov ax,[si].baud
- mov dx,offset b48st ; Assume 4800 baud.
- cmp ax,B4800
- jnz bdprt0
- jmp bdprt2
- bdprt0: mov dx,offset b12st
- cmp ax,B1200
- jnz bdprt1
- jmp bdprt2
- bdprt1: mov dx,offset b18st
- cmp ax,B1800
- jz bdprt2
- mov dx,offset b24st
- cmp ax,B2400
- jz bdprt2
- mov dx,offset b96st
- cmp ax,B9600
- jz bdprt2
- mov dx,offset b03st
- cmp ax,B0300
- jz bdprt2
- mov dx,offset b04st
- cmp ax,B00455
- jz bdprt2
- mov dx,offset b05st
- cmp ax,B0050
- jz bdprt2
- mov dx,offset b07st
- cmp ax,b0075
- jz bdprt2
- mov dx,offset b11st
- cmp ax,B0110
- jz bdprt2
- mov dx,offset b13st
- cmp ax,B01345
- jz bdprt2
- mov dx,offset b15st
- cmp ax,B0150
- jz bdprt2
- mov dx,offset b06st
- cmp ax,B0600
- je bdprt2
- mov dx,offset b20st
- cmp ax,B2000
- jz bdprt2
- mov dx,offset b19st
- cmp ax,B19200
- jz bdprt2
- mov dx,offset b23st
- cmp ax,b23040
- jz bdprt2
- mov dx,offset b38st
- cmp ax,b38400
- jz bdprt2
- mov dx,offset unrec ; Unrecognized baud rate.
- bdprt2: mov si,dx ; this is baud rate
- bdprt3: jmp stms1 ; go copy it and return
- BAUDPRT ENDP
-
- setkey proc near
- call Get_Set_Key_table_size ; Get the size of the table in al
- or al, al ; Any table?
- jne setk0 ; yes, use it
- mov dx,offset ermes5
- jmp reterr ; else print error message
-
- setk0: call Parse_for_Set_Key ; Handle machine-specifically
- jmp r ; Failed
-
- cmp bx,-1 ;[jd] do we have scan code?
- jne setk1 ;[jd] yes, skip this part
-
- mov ah,cmtxt
- mov bx,offset rdbuf ; handy buffer
- mov dx,offset sk1msg
- call comnd
- jmp r ; fail return
- mov si,offset rdbuf ; this is parsed number
- call atoi ; Convert input to real number.
- jmp reterr ; No good.
- mov bx,ax ; put accumulation into bl
- setat3: cmp bx,0 ; is scan code 0?
- jne setk2 ; no, have scan code, look for def
-
- setk1: push bx ; save our scan code
- mov ah,cmcfm
- call comnd
- jmp short setkx ; no good, pop bx and return
- nop ; waste a byte
- pop bx
- ; scan code is in bl, ask for string part
- setk2: push bx
- mov dx,offset defpmp
- call prompt
- mov ah,cmtxt
- mov bx,offset rdbuf
- mov dx,offset sk2msg
- call comnd ; read the definition
- jmp short setkx ; pop bx and fail return
- nop
- mov cl,ah
- mov ch,0 ; set up length of definition
- pop ax ; get scan code back
- mov si,offset rdbuf ; point to definition
- call defkey ; go define the key
- jmp rskp ; and return
- setkx: pop bx ; pop junk off stack
- ret ; and return
- setkey endp
-
- ; Convert input in buffer pointed to by SI to real number which is returned
- ; in AX. Return on failure, return skip on success.
- ATOI PROC NEAR
- mov cl,ah ; Number of chars of input.
- mov ch,0 ; size of string
- jcxz atoi4 ; Fail on no input.
- mov ax,0 ; init sum
- mov bh,0 ; high order of this stays 0.
- atoi0: xchg al,bl ; save current sum
- lodsb ; grab a byte
- cmp al,' ' ; leading space?
- jne atoi1 ; no, continue
- xchg al,bl ; put sum back
- jmp short atoi2 ; and continue loop
- atoi1: cmp al,'9'
- ja atoi3 ; out of range, done
- cmp al,'0'
- jb atoi3
- xchg al,bl ; put sum back into al
- mul ten ; shift one digit
- sub bl,'0' ; convert to binary
- add ax,bx ; add to sum
- atoi2: loop atoi0 ; loop thru all chars
- atoi3: jmp rskp
- atoi4: mov dx,offset erms23 ; complain and return
- ret
- ATOI ENDP
-
- ; addition for capture of raw output
-
- setcpt proc near
- test flags.capflg,0FFH
- jz setcp1 ; no capture file, keep going
- mov dx,offset erms24
- jmp reterr
- setcp1: mov comand.cmcr,0 ; Filename must be specified.
- mov ah,cmifi
- mov dx,offset cptfcb
- mov bx,offset filhlp
- call comnd
- jmp r
- mov ah,cmcfm
- call comnd ; confirm with carriage return
- jmp r
- mov ah,delf
- mov dx,offset cptfcb
- int dos ; open up file
- mov ah,makef
- mov dx,offset cptfcb
- int dos
- mov cptfcb+32,0
-
- call inicpt ; init capture variables
- mov flags.capflg,0FFH ; know we have capture routine
- jmp rskp ; and return
-
- setcpt endp
-
- ; Jumping to this location is like retskp. It assumes the instruction
- ; after the call is a jmp addr.
-
- RSKP PROC NEAR
- pop bp
- add bp,3
- push bp
- ret
- RSKP ENDP
-
- ; Jumping here is the same as a ret.
-
- R PROC NEAR
- ret
- R ENDP
-
- ; routine to print an error message, then retskp
- ; expects message in dx
- reterr proc near
- mov ah,prstr
- int dos
- jmp rskp
- reterr endp
-
- code ends
- end
-